IniOpenFileUnit Subroutine

private subroutine IniOpenFileUnit(fileUnit, iniDB)

read a ini file already open

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: fileUnit
type(IniList), intent(out) :: iniDB

Variables

Type Visibility Attributes Name Initial
integer(kind=long), public :: i
character(len=stringLen), public :: inLine

Source Code

SUBROUTINE IniOpenFileUnit &
!
(fileUnit, iniDB)

IMPLICIT NONE
! subroutine arguments 
! Scalar arguments with intent(in):
INTEGER (KIND = short) , INTENT(IN)  :: fileUnit

! Array arguments with intent(out):
TYPE (IniList), INTENT(OUT)  :: iniDB 

! Local Scalars: 
CHARACTER (LEN = stringLen)     :: inLine
INTEGER (KIND = long)           :: i
!------------end of declaration------------------------------------------------

!------------------------------------------------------------------------------
![1.0] Inizialization:
!------------------------------------------------------------------------------

iniDB % nOfSections = 0
iniDB % nOfSubSections = 0
iniDB % numKeys = 0
numKeys = 0

!count number of keys in  file
iniDB % numKeys = IniCountKeys (fileUnit)

!allocate space
ALLOCATE ( iniDB % keys ( iniDB % numKeys ) )
ALLOCATE ( iniDB % vals ( iniDB % numKeys ) )
ALLOCATE ( iniDB % sectionName ( iniDB % numKeys ) )
ALLOCATE ( iniDB % subSectionName ( iniDB % numKeys ) )
ALLOCATE ( iniDB % sectionBegin ( iniDB % numKeys ) )
ALLOCATE ( iniDB % sectionEnd ( iniDB % numKeys ) )
ALLOCATE ( iniDB % subSectionBegin ( iniDB % numKeys ) )
ALLOCATE ( iniDB % subSectionEnd ( iniDB % numKeys ) )

iniDB % keys = ''
iniDB % vals = ''
iniDB % sectionName = ''
iniDB % subSectionName = ''
iniDB % sectionBegin = 0
iniDB % sectionEnd = 0
iniDB % subSectionBegin = 0
iniDB % subSectionEnd = 0
   
inSection = .FALSE.
inSubSection = .FALSE.

!------------------------------------------------------------------------------
![2.0] Parse ini file to the end of file:
!------------------------------------------------------------------------------
REWIND (fileUnit)
DO 
  READ (fileUnit,'(a)',IOSTAT = ios) inLine
  IF (ios < 0) THEN !end of file encountered
	  CALL CheckClosure(iniDB)
	  EXIT    
  ENDIF
  IF (inLine /= '') CALL IniAddLine(inLine, iniDB) 
END DO


RETURN

END SUBROUTINE IniOpenFileUnit